home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / brklyprl.lha / Emulator / Tests / mergesort.pl < prev    next >
Encoding:
Text File  |  1989-04-14  |  5.5 KB  |  145 lines

  1.  
  2. /* Copyright (C) 1988, 1989 Herve' Touati, Aquarius Project, UC Berkeley */
  3.  
  4. % Merge-Split Parallel Sorting Algorithm
  5. % See: Parallel Sorting Alorithms by Selim G. Akl
  6. %       1985, Toronto, Academic Press
  7. % 20-May-86    Mike Carlton
  8.  
  9. main :- main(50).
  10.  
  11. main(P) :-
  12.    make_list(Unsorted),
  13.    mergesplit(P, Unsorted, Sorted),
  14.    length(Unsorted, L),
  15.    write(L), write(' numbers with '), write(P), write(' processors'), nl,
  16.    write(Sorted), nl.
  17.  
  18. mergesplit(P, Sorted) :-
  19.    atom(P),
  20.    make_list(Unsorted),
  21.    mergesplit(P, Unsorted, Sorted).
  22. mergesplit(Unsorted, Sorted) :-
  23.    get_processors(P),            % Find the number of processes to use
  24.    mergesplit(P, Unsorted, Sorted).
  25. mergesplit(P, Unsorted, Sorted) :-
  26.    binpack(Unsorted, P, Bins),          % Break list into P lists
  27.    binsort(Bins, SortedBins),           % Sort each of the P lists
  28.    mrgsplt(SortedBins, P, NewBins),     % Sort the whole list
  29.    unbinpack(NewBins, Sorted).           % Remove from bins
  30.  
  31. binpack(Unsorted, P, Bins) :-        % Breaks the list Unsorted into P Bins
  32.    makeempty(P, Emptybins),             % Make P empty lists
  33.    bin2(Unsorted, Emptybins, Bins).      % Do the work
  34.  
  35. bin2([], Bins, Bins).             % Stop
  36. bin2(Unsorted, BinsSoFar, Bins) :-      
  37.    bin3(Unsorted, Rest, BinsSoFar, NewBins), % Move 1 elt. from Unsorted to
  38.    bin2(Rest, NewBins, Bins).         % each bin and then do the rest
  39.  
  40. bin3(Rest, Rest, [], []).        % Stop when no more bins
  41. bin3([H1|T1], Rest, [H2|T2], [[H1|H2]|T3]) :-    % Move H1 to head of 1st bin
  42.    bin3(T1, Rest, T2, T3).            % do the rest
  43. bin3([], Rest, [H2|T2], [H2|T3]) :-    % If out of unsorted elts. copy bin
  44.    bin3([], Rest, T2, T3).
  45.  
  46. makeempty(0, []).            % Stop when no more to build
  47. makeempty(Count, [[]|T]) :-        % Add [] to the list
  48.     NewCount is Count-1,        % Decrement
  49.     makeempty(NewCount, T).        % Do the rest
  50.  
  51. binsort([], []).            % Stop when no more
  52. binsort([FirstBin|Bins], [SortedBin|Rest]) :-      % Add the next bin sorted 
  53.    quicksort(FirstBin, SortedBin),    % Sort FirstBin
  54.    binsort(Bins, Rest).             % do the rest
  55.  
  56. quicksort(Unsorted, Sorted) :-        % Quicksort using difference lists
  57.    qsort(Unsorted, Sorted-[]).
  58.  
  59. qsort([], Rest-Rest).            % Stop
  60. qsort([X|Unsorted], Sorted-Rest) :-
  61.    partition(Unsorted, X, Smaller, Larger),    % Partition around 1st elt
  62.    qsort(Smaller, Sorted-[X|Sorted1]),    % Sort the first half
  63.    qsort(Larger, Sorted2-Rest),        % Sort the second half
  64.    Sorted2 = Sorted1.            % Unify ( for parallel qsort calls )
  65.  
  66. partition([], _, [], []).        % Stop
  67. partition([X|Xs], A, Smaller, [X|Larger]) :-    % Add next elt. to larger list
  68.    A < X,                    % if is larger than partition
  69.    partition(Xs, A, Smaller, Larger).        % do the rest
  70. partition([X|Xs], A, [X|Smaller], Larger) :-    % Add next elt. to smaller list
  71.    A >= X,                    % if is smaller than partition    
  72.    partition(Xs, A, Smaller, Larger).        % do the rest
  73.  
  74. mrgsplt(Sorted, 0, Sorted).             % Stop
  75. mrgsplt(Sortedbins, Count, Sorted) :-        % Sort the whole list
  76.    odd(Count),                    % if an odd iteration
  77.    mrgandsplt(Sortedbins,NewSortedBins),    % merge and split once
  78.    NewCount is Count-1,                % decrement
  79.    mrgsplt(NewSortedBins, NewCount, Sorted).     % and do the rest
  80. mrgsplt([First|Sortedbins], Count, Sorted) :-     % Sort the whole list
  81.    even(Count),                    % if an even iteration
  82.    mrgandsplt(Sortedbins,NewSortedBins),    % merge and split once
  83.    NewCount is Count-1,                % decrement
  84.    mrgsplt([First|NewSortedBins], NewCount, Sorted). % and do the rest
  85.  
  86. mrgandsplt([], []).                % Stop when none left
  87. mrgandsplt([Chunk],[Chunk]).            % or if only 1 left
  88. mrgandsplt([Chunk1, Chunk2|Rest], [NewChunk1, NewChunk2|Sorted]) :-
  89.    merge(Chunk1, Chunk2, 0, Length, Chunk),    % merge into Chunk
  90.    split(Chunk, Length, NewChunk1, NewChunk2),  % split Chunk
  91.    mrgandsplt(Rest,Sorted).            % do the rest
  92.  
  93. merge([], [], Len, Len, []).            % merge nothings to nothing
  94. merge(H1, [], OldLen, NewLen, H1) :-        % second list empty
  95.    length(H1, Len),            
  96.    NewLen is OldLen+Len.            % count first list's length
  97. merge([], H2, Len, Len, H2).            % first list empty
  98. merge([H1|T1], [H2|T2], OldLen, NewLen, [H1|T3]) :-
  99.    H1 =< H2,                    % copy from first list
  100.    Len is OldLen+1,                % inc. length
  101.    merge(T1, [H2|T2], Len, NewLen, T3).        % do the rest
  102. merge([H1|T1], [H2|T2], Len, NewLen, [H2|T3]) :-
  103.    H2 < H1,                    % copy from second list
  104.    merge([H1|T1], T2, Len, NewLen, T3).        % do the rest
  105.  
  106. split(Chunk, 0, [], Chunk).
  107. split([H|T], Length, [H|Chunk1], Chunk2) :-
  108.    NewLength is Length-1,
  109.    split(T, NewLength, Chunk1, Chunk2).
  110.    
  111. make_list([50,48,46,44,42,40,38,36,34,32,30,28,26,24,22,20,18,
  112.        16,14,12,10, 8, 6, 4, 2, 1, 3, 5, 7, 9,11,13,15,17,
  113.        19,21,23,25,27,29,31,33,35,37,39,41,43,45,47,49,
  114.            50,48,46,44,42,40,38,36,34,32,30,28,26,24,22,20,18,
  115.        16,14,12,10, 8, 6, 4, 2, 1, 3, 5, 7, 9,11,13,15,17,
  116.        19,21,23,25,27,29,31,33,35,37,39,41,43,45,47,49,
  117.            50,48,46,44,42,40,38,36,34,32,30,28,26,24,22,20,18,
  118.        16,14,12,10, 8, 6, 4, 2, 1, 3, 5, 7, 9,11,13,15,17,
  119.        19,21,23,25,27,29,31,33,35,37,39,41,43,45,47,49,
  120.            50,48,46,44,42,40,38,36,34,32,30,28,26,24,22,20,18,
  121.        16,14,12,10, 8, 6, 4, 2, 1, 3, 5, 7, 9,11,13,15,17,
  122.        19,21,23,25,27,29,31,33,35,37,39,41,43,45,47,49,
  123.            50,48,46,44,42,40,38,36,34,32,30,28,26,24,22,20,18,
  124.        16,14,12,10, 8, 6, 4, 2, 1, 3, 5, 7, 9,11,13,15,17,
  125.        19,21,23,25,27,29,31,33,35,37,39,41,43,45,47,49]).
  126. get_processors(3).                % number of processors
  127.  
  128. unbinpack(Bins, UnBins) :-
  129.    unbinpack(Bins, [], UnBins).
  130. unbinpack([], SoFar, SoFar).
  131. unbinpack([H|T], SoFar, UnBins) :-
  132.    append(SoFar, H, NewSoFar),
  133.    unbinpack(T, NewSoFar, UnBins).
  134.  
  135. append([], L, L).
  136. append([X|L1], L2, [X|L3]) :-
  137.    append(L1, L2, L3).
  138.  
  139. even(N) :-
  140.    0 is N mod 2.
  141.  
  142. odd(N) :-
  143.    1 is N mod 2.
  144.  
  145.